home *** CD-ROM | disk | FTP | other *** search
/ Language/OS - Multiplatform Resource Library / LANGUAGE OS.iso / prolog / sbprolog / amiga / v3_1 / sbp3_1e.lzh / READNUM.PL < prev    next >
Text File  |  1991-10-31  |  4KB  |  95 lines

  1. /* From the book PROLOG PROGRAMMING IN DEPTH
  2.    by Michael A. Covington, Donald Nute, and Andre Vellino.
  3.    Copyright 1988 Scott, Foresman & Co.
  4.    Non-commercial distribution of this file is permitted. */
  5.  
  6. /* READNUM.PL */
  7. /* Input procedure for integers and floating-point numbers */
  8.  
  9. /* Requires procedure READSTRING defined in file READSTR.PL */
  10. :- ( clause(readstring(_),_) ; consult('readstr.pl') ).
  11.  
  12. /* This is Arity and Quintus Prolog. Minor changes will probably be
  13.  * required in other Prologs because of differences in arithmetic. */
  14.  
  15. /**********************************************************************
  16.  * readnumber(Result)                                                 *
  17.  *   Accepts a string from the user and interprets it as a number     *
  18.  *   (integer or floating point). Negative numbers are accepted;      *
  19.  *   E format is not.                                                 *
  20.  **********************************************************************/
  21.  
  22. readnumber(Result) :- readstring(S),
  23.                       nl,
  24.                       readnumber_start(S,Result).
  25.  
  26. /* readnumber_start(String,Result)
  27.  *    checks for initial blanks or minus sign, then passes
  28.  *    control to readnumber_aux with state variables initialized.
  29.  */
  30.  
  31. readnumber_start([32|Tail],Result) :-    /* discard leading blanks */
  32.                     !,
  33.                     readnumber_start(Tail,Result).
  34.  
  35. readnumber_start([45|Tail],Result) :-    /* begins with minus sign */
  36.                     !,
  37.                     readnumber_aux(Tail,no,-1,0,Result).
  38.  
  39. readnumber_start(String,Result) :-       /* does not begin with minus */
  40.                     readnumber_aux(String,no,1,0,Result).
  41.  
  42. /* readnumber_aux(String,Point,Divisor,SoFar,Result)
  43.  *    works through String one character at a time.
  44.  *    Point is 'yes' if the point has been found, 'no' if not.
  45.  *    Divisor is 1 until the point is encountered, after
  46.  *    which it becomes 10, 100, etc., in succession.
  47.  *    If number is negative, divisor is -1, -10, etc.
  48.  *    SoFar represents the part of the number already read.
  49.  */
  50.  
  51. readnumber_aux([Digit|Tail],no,Divisor,SoFar,Result) :-
  52.           readnumber_value(Digit,Value),
  53.           !,                       /* a digit to the left of the point */
  54.           NewSoFar is SoFar*10 + Value,
  55.           readnumber_aux(Tail,no,Divisor,NewSoFar,Result).
  56.  
  57. readnumber_aux([46|Tail],no,Divisor,SoFar,Result) :-
  58.           !,                       /* the decimal point itself */
  59.           readnumber_aux(Tail,yes,Divisor,SoFar,Result).
  60.  
  61. readnumber_aux([Digit|Tail],yes,Divisor,SoFar,Result) :-
  62.           readnumber_value(Digit,Value),
  63.           !,                       /* a digit to the right of the point */
  64.           NewSoFar is SoFar*10 + Value,
  65.           NewDivisor is Divisor*10,
  66.           readnumber_aux(Tail,yes,NewDivisor,NewSoFar,Result).
  67.  
  68. readnumber_aux([],_,1,Result,Result) :- !. /* all done, positive integer */
  69.  
  70. readnumber_aux([],_,-1,SoFar,Result) :- !, /* all done, negative integer */
  71.                                         Result is -(SoFar).
  72.  
  73. readnumber_aux([],yes,Divisor,SoFar,Result) :-
  74.           !,                            /* all done, it's floating point */
  75.           Result is SoFar/Divisor.
  76.  
  77. readnumber_aux(_,_,_,_,Result) :-      /* unrecognized character */
  78.           write('Number expected. Try again:'),
  79.           readnumber(Result).
  80.  
  81. /* readnumber_value(ASCII,Number)
  82.  *   converts ASCII codes of digits to numeric values.
  83.  */
  84.  
  85. readnumber_value(48,0).
  86. readnumber_value(49,1).
  87. readnumber_value(50,2).
  88. readnumber_value(51,3).
  89. readnumber_value(52,4).
  90. readnumber_value(53,5).
  91. readnumber_value(54,6).
  92. readnumber_value(55,7).
  93. readnumber_value(56,8).
  94. readnumber_value(57,9).
  95.